home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / manchest.lha / MANCHESTER / manchester / 2.2 / Lock.st < prev    next >
Text File  |  1993-07-24  |  11KB  |  348 lines

  1. "    NAME        Lock
  2.     AUTHOR        tph@cs.man.ac.uk
  3.     FUNCTION locks the screen with a background pattern 
  4.     ST-VERSIONS    2.2
  5.     PREREQUISITES    Raindrop 
  6.     CONFLICTS    
  7.     DISTRIBUTION      world
  8.     VERSION        1.1
  9.     DATE    22 Jan 1989
  10. SUMMARY    Lock
  11.     contains a goodie which mimics the Suntools ""lockscreen""
  12.    utility.  Three different lockscreen patterns are provided.  You
  13.    require Raindrop.st before filing this one in. (2.2). TPH.
  14. "!
  15. 'From Smalltalk-80, version 2, of April 1, 1983 on 22 February 1987 at 3:01:55 pm'!
  16.  
  17. Smalltalk at: #LockScreenRunning put: false!
  18.  
  19. !Number methodsFor: 'testing'!
  20.  
  21. signPositive
  22.     "Answer 1 if the receiver is greater than 0 else -1."
  23.  
  24.     self >= 0
  25.         ifTrue: [^1]
  26.         ifFalse: [^-1]! !'From Smalltalk-80, version 2, of April 1, 1983 on 19 February 1987 at 9:06:31 pm'!
  27.  
  28.  
  29.  
  30. !InputState methodsFor: 'private'!
  31.  
  32. keyAt: keyNumber put: value
  33.     | index mask |
  34.     index _ keyNumber < 8r200 ifTrue: [KeyboardMap at: keyNumber + 1] ifFalse: [keyNumber].
  35.     index < 8r200
  36.       ifTrue:  "Not a potential special character"
  37.         [value ~= 0 ifTrue:
  38.             [(ctrlState ~= 0 and: [index = LetterCKey or: [index = $d asciiValue]])
  39.                 ifTrue: [LockScreenRunning ifFalse: [
  40.                         index = LetterCKey
  41.                             ifTrue: [lshiftState ~= 0
  42.                                         ifTrue: [self forkEmergencyEvaluatorAt: Processor userInterruptPriority]
  43.                                         ifFalse: [[ScheduledControllers interruptName: 'User Interrupt'] fork]]
  44.                             ifFalse: [lshiftState ~= 0
  45.                                         ifTrue: [[self doScreenDump] forkAt: Processor userInterruptPriority]]]]
  46.                 ifFalse: [^keyboardQueue nextPut:
  47.                                 (KeyboardEvent code: keyNumber
  48.                                                  meta: metaState)]]]
  49.       ifFalse:
  50.         [index = CtrlKey
  51.           ifTrue: [ctrlState _ value bitShift: 1]
  52.           ifFalse:
  53.             [index = LshiftKey
  54.               ifTrue: [lshiftState _ value]
  55.               ifFalse:
  56.                 [index = RshiftKey
  57.                   ifTrue: [rshiftState _ value]
  58.                   ifFalse:
  59.                     [index = LockKey
  60.                       ifTrue: [lockState _ value bitShift: 2]
  61.                       ifFalse:
  62.                         [(index >= BitMin and: [index <= BitMax])
  63.                           ifTrue:
  64.                             [mask _ 1 bitShift: index - BitMin.
  65.                             value = 1
  66.                               ifTrue: [bitState _ bitState bitOr: mask]
  67.                               ifFalse: [bitState _ bitState bitAnd: -1 - mask]]
  68.                           ifFalse:
  69.                             [value ~= 0 ifTrue:
  70.                                 [keyboardQueue nextPut:
  71.                                     (KeyboardEvent code: keyNumber meta: metaState)]]]]]].
  72.         metaState _ (ctrlState bitOr: (lshiftState bitOr: rshiftState)) bitOr: lockState]! !'From Smalltalk-80, version 2, of April 1, 1983 on 22 February 1987 at 3:01:10 pm'!
  73.  
  74. CRFillInTheBlankController subclass: #LockscreenBlankController
  75.     instanceVariableNames: ''
  76.     classVariableNames: ''
  77.     poolDictionaries: ''
  78.     category: 'Interface-Prompt/Confirm'!
  79.  
  80.  
  81. !LockscreenBlankController methodsFor: 'private'!
  82.  
  83. initializeYellowButtonMenu
  84.  
  85.     self yellowButtonMenu: nil
  86.         yellowButtonMessages: nil! !'From Smalltalk-80, version 2, of April 1, 1983 on 22 February 1987 at 3:01:13 pm'!
  87.  
  88. FillInTheBlankView subclass: #LockscreenBlankView
  89.     instanceVariableNames: ''
  90.     classVariableNames: ''
  91.     poolDictionaries: ''
  92.     category: 'Interface-Prompt/Confirm'!
  93.  
  94. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  95.  
  96. LockscreenBlankView class
  97.     instanceVariableNames: ''!
  98.  
  99.  
  100. !LockscreenBlankView class methodsFor: 'instance creation'!
  101.  
  102. on: aFillInTheBlank message: messageString displayAt: originPoint centered: centered
  103.  
  104.     | topView messageView answerView |
  105.     messageView _ self buildMessageView: messageString.
  106.     answerView _ 
  107.         self buildAnswerView: aFillInTheBlank 
  108.             frameWidth: messageView window width.
  109.     answerView controller: LockscreenBlankController new.
  110.     topView _ View new model: aFillInTheBlank.
  111.     topView controller: BinaryChoiceController new.
  112.     topView addSubView: messageView.
  113.     topView addSubView: answerView below: messageView.
  114.     topView align: (centered
  115.             ifTrue: [topView viewport center]
  116.             ifFalse: [topView viewport topLeft])
  117.         with: originPoint.
  118.     topView window: 
  119.         (0 @ 0 extent: 
  120.             messageView window width @ 
  121.             (messageView window height + answerView window height)).
  122.     topView translateBy:
  123.         (topView displayBox amountToTranslateWithin: Display boundingBox).
  124.     ^topView! !'From Smalltalk-80, version 2, of April 1, 1983 on 22 February 1987 at 3:01:06 pm'!
  125.  
  126. FillInTheBlank subclass: #LockscreenBlank
  127.     instanceVariableNames: ''
  128.     classVariableNames: ''
  129.     poolDictionaries: ''
  130.     category: 'Interface-Prompt/Confirm'!
  131.  
  132. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  133.  
  134. LockscreenBlank class
  135.     instanceVariableNames: ''!
  136.  
  137.  
  138. !LockscreenBlank class methodsFor: 'instance creation'!
  139.  
  140. request: messageString displayAt: aPoint centered: centered action: aBlock initialAnswer: aString
  141.     "Answer an instance of me whose question is messageString.  Once the user provides an answer, then evaluate aBlock. If centered, a Boolean, is false, display the view of the instance at aPoint; otherwise display it with its center at aPoint. "
  142.  
  143.     | newBlank fillInView savedArea |
  144.     newBlank _ self new initialize.
  145.     newBlank action: aBlock.
  146.     newBlank contents: aString.
  147.     fillInView _ 
  148.         LockscreenBlankView
  149.             on: newBlank
  150.             message: messageString
  151.             displayAt: aPoint
  152.             centered: centered.
  153.     savedArea _ Form fromDisplay: fillInView displayBox.
  154.     fillInView display.
  155.     fillInView controller centerCursorInView.
  156.     fillInView controller startUp.
  157.     fillInView release.
  158.     savedArea displayOn: Display at: fillInView viewport topLeft! !'From Smalltalk-80, version 2, of April 1, 1983 on 22 February 1987 at 3:01:19 pm'!
  159.  
  160. Object subclass: #LockScreen
  161.     instanceVariableNames: 'startBlock doBlock endBlock '
  162.     classVariableNames: ''
  163.     poolDictionaries: ''
  164.     category: 'Graphics-Games'!
  165. LockScreen comment:
  166. 'I am a class where instances of me permit the screen to be "locked"
  167. i.e. access to the machine is barred unless the user demonstrates the knowledge
  168. of the password previously typed.
  169.  
  170. When created, I have three instance variables, all of which are blocks.
  171.  
  172. <startBlock> This block is executed when my instance is invoked, and
  173.               after a failed attempt to type a password.  Typically, this
  174.               block clears the display.
  175.  
  176. <doBlock>      This block is executed repeatedly.
  177.  
  178. <endBlock>      This block is executed once after a password is correctly typed.
  179.               Typically, this restores the display.
  180.  
  181. I also have class variables, which are the default blocks used.
  182. '!
  183.  
  184.  
  185. !LockScreen methodsFor: 'accessing'!
  186.  
  187. doBlock
  188.     "Answer the block to be executed by the lockscreen."
  189.  
  190.     ^doBlock!
  191.  
  192. doBlock: aBlock
  193.     "Sets the block to be executed by the lockscreen."
  194.  
  195.     doBlock _ aBlock!
  196.  
  197. endBlock
  198.     "Answer the block to be executed after the lockscreen finishes."
  199.  
  200.     ^endBlock!
  201.  
  202. endBlock: aBlock
  203.     "Set the block to be executed after the lockscreen finishes."
  204.  
  205.     endBlock _ aBlock!
  206.  
  207. startBlock
  208.     "Answer the block to be executed before the lockscreen starts."
  209.  
  210.     ^startBlock!
  211.  
  212. startBlock: aBlock
  213.     "Set the block to be executed before the lockscreen starts."
  214.  
  215.     startBlock _ aBlock! !
  216.  
  217. !LockScreen methodsFor: 'execution'!
  218.  
  219. doIt
  220.     "Actual code for the lockscreen."
  221.  
  222.     | password anotherPassword |
  223.     password _ FillInTheBlank request: 'Type Password'.
  224.     anotherPassword _ FillInTheBlank request: 'Type Password again'.
  225.     (password ~= anotherPassword)
  226.         ifTrue: [
  227.             Display reverse.
  228.             (Delay forMilliseconds: 400) wait.
  229.             Display reverse]
  230.         ifFalse: [
  231.             anotherPassword _ nil.
  232.             LockScreenRunning _ true.
  233.             Cursor blank showWhile: [
  234.                 [anotherPassword = password] whileFalse: [
  235.                     self startBlock value.
  236.                     [Sensor noButtonPressed] whileTrue: [self doBlock value].
  237.                     Sensor flushKeyboard.
  238.                     (Delay forSeconds: 3) wait.
  239.                     anotherPassword _ LockscreenBlank request: 'Type Password followed by <CR>']].
  240.             self endBlock value.
  241.             LockScreenRunning _ false].! !
  242. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  243.  
  244. LockScreen class
  245.     instanceVariableNames: ''!
  246.  
  247.  
  248. !LockScreen class methodsFor: 'instance creation'!
  249.  
  250. doIt
  251.     "Starts the lockscreen, with the default blocks."
  252.  
  253.     self raindrop!
  254.  
  255. new: stBlock do: aBlock end: eBlock
  256.     "Create a new instance of me, with startBlock as the startup block,
  257.      aBlock as the normal execution block, and endBlock as the ending code."
  258.  
  259.     | temp |
  260.     temp _ super new startBlock: stBlock.
  261.     temp doBlock: aBlock.
  262.     temp endBlock: eBlock.
  263.     ^temp! !
  264.  
  265. !LockScreen class methodsFor: 'examples'!
  266.  
  267. mandala
  268.     "Start a lockscreen, with a mandala display."
  269.  
  270.     "LockScreen mandala."
  271.  
  272.     | temp aPen anArray index delay |
  273.     temp _ self new: [
  274.         Display white.
  275.         delay _ Delay forSeconds: 1.2.
  276.         aPen _ Pen new defaultNib: 1.
  277.         anArray _ #(5 6 8 9 10 12 15 20 30).
  278.         index _ 1]
  279.     do: [aPen mandala: (anArray at: index) diameter: 750.
  280.          (index = anArray size)
  281.             ifTrue: [index _ 1]
  282.             ifFalse: [index _ index + 1].
  283.          delay wait]
  284.     end: [ScheduledControllers restore].
  285.     temp doIt!
  286.  
  287. raindrop
  288.     "Start a lockscreen, with a raindrop display."
  289.  
  290.     "LockScreen raindrop."
  291.  
  292.     | temp exampleRain r |
  293.     temp _ self new: [
  294.         Display white.
  295.         exampleRain _ Raindrop
  296.                     new: 20
  297.                     maxExtent: 180
  298.                     penWidth: 4
  299.                     minExtent: 15
  300.                     mask: #black.
  301.         r _ Random new]
  302.     do: [[exampleRain centre: r next * Display width @
  303.                 (r next * Display height) delayedForSeconds: 0.2] fork.
  304.         (Delay forSeconds: 0.1) wait]
  305.     end: [ScheduledControllers restore].
  306.     temp doIt!
  307.  
  308. worm
  309.     "Start a lockscreen, with a worm display."
  310.  
  311.     "LockScreen worm."
  312.  
  313.     | random box temp sign facade outliner queue point delta |
  314.     facade _ Form
  315.         extent: 20@20
  316.         fromArray: #(65471 61440 63191 61440 64699 61440 57453 61440 55307
  317.             28672 61463 61440 53285 28672 47123 61440 54493 61440 65191 28672
  318.             53981 61440 48983 61440 62847 61440 65517 61440 61151 61440 65407
  319.             61440 65535 61440 65535 61440 65535 61440 65535 61440)
  320.         offset: -10@-10.
  321.     box _ Display boundingBox insetBy: 18@18.
  322.     outliner _ Form dotOfSize: facade extent x + 4.
  323.     queue _ SharedQueue new: 32.
  324.     16 timesRepeat: [queue nextPut: 0@0].
  325.     random _ Random new.
  326.     temp _ self
  327.         new: [point _ 100@100.
  328.               delta _ 0@0.
  329.               Display white]
  330.         do: [outliner displayOn: Display at: point rule: Form under.
  331.             facade displayOn: Display at: queue next rule: Form and.
  332.             queue nextPut: point.
  333.             (random next > 0.75) & (delta x abs < 10)
  334.                 ifTrue: [delta x: (delta x signPositive) * (delta x abs + 1)].
  335.             (random next > 0.75) & (delta x abs > 0)
  336.                 ifTrue: [delta x: (delta x signPositive) * (delta x abs - 1)].
  337.             (random next > 0.75) & (delta y abs < 10)
  338.                 ifTrue: [delta y: (delta y signPositive) * (delta y abs + 1)].
  339.             (random next > 0.75) & (delta y abs > 0)
  340.                 ifTrue: [delta y: (delta y signPositive) * (delta y abs - 1)].
  341.             ((point + delta) x >  box right) ifTrue: [delta x: (delta x - 3)].
  342.             ((point + delta) x < box left) ifTrue: [delta x: (delta x + 3)].
  343.             ((point + delta) y > box bottom) ifTrue: [delta y: (delta y - 3)].
  344.             ((point + delta) y < box top) ifTrue: [delta y: (delta y + 3)].
  345.             point _ point + delta]
  346.     end: [ScheduledControllers restore].
  347.     temp doIt! !
  348.